home *** CD-ROM | disk | FTP | other *** search
/ IRIX Base Documentation 2002 November / SGI IRIX Base Documentation 2002 November.iso / usr / share / catman / p_man / cat3 / SCSL / zgesvx.z / zgesvx
Encoding:
Text File  |  2002-10-03  |  13.8 KB  |  331 lines

  1.  
  2.  
  3.  
  4. ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))                                                          ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))
  5.  
  6.  
  7.  
  8. NNNNAAAAMMMMEEEE
  9.      ZGESVX - use the LU factorization to compute the solution to a complex
  10.      system of linear equations A * X = B,
  11.  
  12. SSSSYYYYNNNNOOOOPPPPSSSSIIIISSSS
  13.      SUBROUTINE ZGESVX( FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED,
  14.                         R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK,
  15.                         INFO )
  16.  
  17.          CHARACTER      EQUED, FACT, TRANS
  18.  
  19.          INTEGER        INFO, LDA, LDAF, LDB, LDX, N, NRHS
  20.  
  21.          DOUBLE         PRECISION RCOND
  22.  
  23.          INTEGER        IPIV( * )
  24.  
  25.          DOUBLE         PRECISION BERR( * ), C( * ), FERR( * ), R( * ), RWORK(
  26.                         * )
  27.  
  28.          COMPLEX*16     A( LDA, * ), AF( LDAF, * ), B( LDB, * ), WORK( * ), X(
  29.                         LDX, * )
  30.  
  31. IIIIMMMMPPPPLLLLEEEEMMMMEEEENNNNTTTTAAAATTTTIIIIOOOONNNN
  32.      These routines are part of the SCSL Scientific Library and can be loaded
  33.      using either the -lscs or the -lscs_mp option.  The -lscs_mp option
  34.      directs the linker to use the multi-processor version of the library.
  35.  
  36.      When linking to SCSL with -lscs or -lscs_mp, the default integer size is
  37.      4 bytes (32 bits). Another version of SCSL is available in which integers
  38.      are 8 bytes (64 bits).  This version allows the user access to larger
  39.      memory sizes and helps when porting legacy Cray codes.  It can be loaded
  40.      by using the -lscs_i8 option or the -lscs_i8_mp option. A program may use
  41.      only one of the two versions; 4-byte integer and 8-byte integer library
  42.      calls cannot be mixed.
  43.  
  44. PPPPUUUURRRRPPPPOOOOSSSSEEEE
  45.      ZGESVX uses the LU factorization to compute the solution to a complex
  46.      system of linear equations A * X = B, where A is an N-by-N matrix and X
  47.      and B are N-by-NRHS matrices.
  48.  
  49.      Error bounds on the solution and a condition estimate are also provided.
  50.  
  51.  
  52. DDDDEEEESSSSCCCCRRRRIIIIPPPPTTTTIIIIOOOONNNN
  53.      The following steps are performed:
  54.  
  55.      1. If FACT = 'E', real scaling factors are computed to equilibrate
  56.         the system:
  57.            TRANS = 'N':  diag(R)*A*diag(C)     *inv(diag(C))*X = diag(R)*B
  58.            TRANS = 'T': (diag(R)*A*diag(C))**T *inv(diag(R))*X = diag(C)*B
  59.            TRANS = 'C': (diag(R)*A*diag(C))**H *inv(diag(R))*X = diag(C)*B
  60.  
  61.  
  62.  
  63.                                                                         PPPPaaaaggggeeee 1111
  64.  
  65.  
  66.  
  67.  
  68.  
  69.  
  70. ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))                                                          ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))
  71.  
  72.  
  73.  
  74.         Whether or not the system will be equilibrated depends on the
  75.         scaling of the matrix A, but if equilibration is used, A is
  76.         overwritten by diag(R)*A*diag(C) and B by diag(R)*B (if TRANS='N')
  77.         or diag(C)*B (if TRANS = 'T' or 'C').
  78.  
  79.      2. If FACT = 'N' or 'E', the LU decomposition is used to factor the
  80.         matrix A (after equilibration if FACT = 'E') as
  81.            A = P * L * U,
  82.         where P is a permutation matrix, L is a unit lower triangular
  83.         matrix, and U is upper triangular.
  84.  
  85.      3. If some U(i,i)=0, so that U is exactly singular, then the routine
  86.         returns with INFO = i. Otherwise, the factored form of A is used
  87.         to estimate the condition number of the matrix A.  If the
  88.         reciprocal of the condition number is less than machine precision,
  89.         INFO = N+1 is returned as a warning, but the routine still goes on
  90.         to solve for X and compute error bounds as described below.
  91.  
  92.      4. The system of equations is solved for X using the factored form
  93.         of A.
  94.  
  95.      5. Iterative refinement is applied to improve the computed solution
  96.         matrix and calculate error bounds and backward error estimates
  97.         for it.
  98.  
  99.      6. If equilibration was used, the matrix X is premultiplied by
  100.         diag(C) (if TRANS = 'N') or diag(R) (if TRANS = 'T' or 'C') so
  101.         that it solves the original system before equilibration.
  102.  
  103.  
  104. AAAARRRRGGGGUUUUMMMMEEEENNNNTTTTSSSS
  105.      FACT    (input) CHARACTER*1
  106.              Specifies whether or not the factored form of the matrix A is
  107.              supplied on entry, and if not, whether the matrix A should be
  108.              equilibrated before it is factored.  = 'F':  On entry, AF and
  109.              IPIV contain the factored form of A.  If EQUED is not 'N', the
  110.              matrix A has been equilibrated with scaling factors given by R
  111.              and C.  A, AF, and IPIV are not modified.  = 'N':  The matrix A
  112.              will be copied to AF and factored.
  113.              = 'E':  The matrix A will be equilibrated if necessary, then
  114.              copied to AF and factored.
  115.  
  116.      TRANS   (input) CHARACTER*1
  117.              Specifies the form of the system of equations:
  118.              = 'N':  A * X = B     (No transpose)
  119.              = 'T':  A**T * X = B  (Transpose)
  120.              = 'C':  A**H * X = B  (Conjugate transpose)
  121.  
  122.      N       (input) INTEGER
  123.              The number of linear equations, i.e., the order of the matrix A.
  124.              N >= 0.
  125.  
  126.  
  127.  
  128.  
  129.                                                                         PPPPaaaaggggeeee 2222
  130.  
  131.  
  132.  
  133.  
  134.  
  135.  
  136. ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))                                                          ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))
  137.  
  138.  
  139.  
  140.      NRHS    (input) INTEGER
  141.              The number of right hand sides, i.e., the number of columns of
  142.              the matrices B and X.  NRHS >= 0.
  143.  
  144.      A       (input/output) COMPLEX*16 array, dimension (LDA,N)
  145.              On entry, the N-by-N matrix A.  If FACT = 'F' and EQUED is not
  146.              'N', then A must have been equilibrated by the scaling factors in
  147.              R and/or C.  A is not modified if FACT = 'F' or
  148.  
  149.              On exit, if EQUED .ne. 'N', A is scaled as follows:  EQUED = 'R':
  150.              A := diag(R) * A
  151.              EQUED = 'C':  A := A * diag(C)
  152.              EQUED = 'B':  A := diag(R) * A * diag(C).
  153.  
  154.      LDA     (input) INTEGER
  155.              The leading dimension of the array A.  LDA >= max(1,N).
  156.  
  157.      AF      (input or output) COMPLEX*16 array, dimension (LDAF,N)
  158.              If FACT = 'F', then AF is an input argument and on entry contains
  159.              the factors L and U from the factorization A = P*L*U as computed
  160.              by ZGETRF.  If EQUED .ne. 'N', then AF is the factored form of
  161.              the equilibrated matrix A.
  162.  
  163.              If FACT = 'N', then AF is an output argument and on exit returns
  164.              the factors L and U from the factorization A = P*L*U of the
  165.              original matrix A.
  166.  
  167.              If FACT = 'E', then AF is an output argument and on exit returns
  168.              the factors L and U from the factorization A = P*L*U of the
  169.              equilibrated matrix A (see the description of A for the form of
  170.              the equilibrated matrix).
  171.  
  172.      LDAF    (input) INTEGER
  173.              The leading dimension of the array AF.  LDAF >= max(1,N).
  174.  
  175.      IPIV    (input or output) INTEGER array, dimension (N)
  176.              If FACT = 'F', then IPIV is an input argument and on entry
  177.              contains the pivot indices from the factorization A = P*L*U as
  178.              computed by ZGETRF; row i of the matrix was interchanged with row
  179.              IPIV(i).
  180.  
  181.              If FACT = 'N', then IPIV is an output argument and on exit
  182.              contains the pivot indices from the factorization A = P*L*U of
  183.              the original matrix A.
  184.  
  185.              If FACT = 'E', then IPIV is an output argument and on exit
  186.              contains the pivot indices from the factorization A = P*L*U of
  187.              the equilibrated matrix A.
  188.  
  189.      EQUED   (input or output) CHARACTER*1
  190.              Specifies the form of equilibration that was done.  = 'N':  No
  191.              equilibration (always true if FACT = 'N').
  192.  
  193.  
  194.  
  195.                                                                         PPPPaaaaggggeeee 3333
  196.  
  197.  
  198.  
  199.  
  200.  
  201.  
  202. ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))                                                          ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))
  203.  
  204.  
  205.  
  206.              = 'R':  Row equilibration, i.e., A has been premultiplied by
  207.              diag(R).  = 'C':  Column equilibration, i.e., A has been
  208.              postmultiplied by diag(C).  = 'B':  Both row and column
  209.              equilibration, i.e., A has been replaced by diag(R) * A *
  210.              diag(C).  EQUED is an input argument if FACT = 'F'; otherwise, it
  211.              is an output argument.
  212.  
  213.      R       (input or output) DOUBLE PRECISION array, dimension (N)
  214.              The row scale factors for A.  If EQUED = 'R' or 'B', A is
  215.              multiplied on the left by diag(R); if EQUED = 'N' or 'C', R is
  216.              not accessed.  R is an input argument if FACT = 'F'; otherwise, R
  217.              is an output argument.  If FACT = 'F' and EQUED = 'R' or 'B',
  218.              each element of R must be positive.
  219.  
  220.      C       (input or output) DOUBLE PRECISION array, dimension (N)
  221.              The column scale factors for A.  If EQUED = 'C' or 'B', A is
  222.              multiplied on the right by diag(C); if EQUED = 'N' or 'R', C is
  223.              not accessed.  C is an input argument if FACT = 'F'; otherwise, C
  224.              is an output argument.  If FACT = 'F' and EQUED = 'C' or 'B',
  225.              each element of C must be positive.
  226.  
  227.      B       (input/output) COMPLEX*16 array, dimension (LDB,NRHS)
  228.              On entry, the N-by-NRHS right hand side matrix B.  On exit, if
  229.              EQUED = 'N', B is not modified; if TRANS = 'N' and EQUED = 'R' or
  230.              'B', B is overwritten by diag(R)*B; if TRANS = 'T' or 'C' and
  231.              EQUED = 'C' or 'B', B is overwritten by diag(C)*B.
  232.  
  233.      LDB     (input) INTEGER
  234.              The leading dimension of the array B.  LDB >= max(1,N).
  235.  
  236.      X       (output) COMPLEX*16 array, dimension (LDX,NRHS)
  237.              If INFO = 0 or INFO = N+1, the N-by-NRHS solution matrix X to the
  238.              original system of equations.  Note that A and B are modified on
  239.              exit if EQUED .ne. 'N', and the solution to the equilibrated
  240.              system is inv(diag(C))*X if TRANS = 'N' and EQUED = 'C' or 'B',
  241.              or inv(diag(R))*X if TRANS = 'T' or 'C' and EQUED = 'R' or 'B'.
  242.  
  243.      LDX     (input) INTEGER
  244.              The leading dimension of the array X.  LDX >= max(1,N).
  245.  
  246.      RCOND   (output) DOUBLE PRECISION
  247.              The estimate of the reciprocal condition number of the matrix A
  248.              after equilibration (if done).  If RCOND is less than the machine
  249.              precision (in particular, if RCOND = 0), the matrix is singular
  250.              to working precision.  This condition is indicated by a return
  251.              code of INFO > 0.
  252.  
  253.      FERR    (output) DOUBLE PRECISION array, dimension (NRHS)
  254.              The estimated forward error bound for each solution vector X(j)
  255.              (the j-th column of the solution matrix X).  If XTRUE is the true
  256.              solution corresponding to X(j), FERR(j) is an estimated upper
  257.              bound for the magnitude of the largest element in (X(j) - XTRUE)
  258.  
  259.  
  260.  
  261.                                                                         PPPPaaaaggggeeee 4444
  262.  
  263.  
  264.  
  265.  
  266.  
  267.  
  268. ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))                                                          ZZZZGGGGEEEESSSSVVVVXXXX((((3333SSSS))))
  269.  
  270.  
  271.  
  272.              divided by the magnitude of the largest element in X(j).  The
  273.              estimate is as reliable as the estimate for RCOND, and is almost
  274.              always a slight overestimate of the true error.
  275.  
  276.      BERR    (output) DOUBLE PRECISION array, dimension (NRHS)
  277.              The componentwise relative backward error of each solution vector
  278.              X(j) (i.e., the smallest relative change in any element of A or B
  279.              that makes X(j) an exact solution).
  280.  
  281.      WORK    (workspace) COMPLEX*16 array, dimension (2*N)
  282.  
  283.      RWORK   (workspace/output) DOUBLE PRECISION array, dimension (2*N)
  284.              On exit, RWORK(1) contains the reciprocal pivot growth factor
  285.              norm(A)/norm(U). The "max absolute element" norm is used. If
  286.              RWORK(1) is much less than 1, then the stability of the LU
  287.              factorization of the (equilibrated) matrix A could be poor. This
  288.              also means that the solution X, condition estimator RCOND, and
  289.              forward error bound FERR could be unreliable. If factorization
  290.              fails with 0<INFO<=N, then RWORK(1) contains the reciprocal pivot
  291.              growth factor for the leading INFO columns of A.
  292.  
  293.      INFO    (output) INTEGER
  294.              = 0:  successful exit
  295.              < 0:  if INFO = -i, the i-th argument had an illegal value
  296.              > 0:  if INFO = i, and i is
  297.              <= N:  U(i,i) is exactly zero.  The factorization has been
  298.              completed, but the factor U is exactly singular, so the solution
  299.              and error bounds could not be computed. RCOND = 0 is returned.  =
  300.              N+1: U is nonsingular, but RCOND is less than machine precision,
  301.              meaning that the matrix is singular to working precision.
  302.              Nevertheless, the solution and error bounds are computed because
  303.              there are a number of situations where the computed solution can
  304.              be more accurate than the value of RCOND would suggest.
  305.  
  306. SSSSEEEEEEEE AAAALLLLSSSSOOOO
  307.      INTRO_LAPACK(3S), INTRO_SCSL(3S)
  308.  
  309.      This man page is available only online.
  310.  
  311.  
  312.  
  313.  
  314.  
  315.  
  316.  
  317.  
  318.  
  319.  
  320.  
  321.  
  322.  
  323.  
  324.  
  325.  
  326.  
  327.                                                                         PPPPaaaaggggeeee 5555
  328.  
  329.  
  330.  
  331.